home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Speccy ClassiX 1998
/
Speccy ClassiX 98.iso
/
amiga_system
/
the_aminet
/
dev
/
gcc
/
ixemulsrc.lha
/
ixemul-41.4
/
stdlib
/
execve.c
< prev
next >
Wrap
C/C++ Source or Header
|
1995-10-01
|
19KB
|
664 lines
/*
* This file is part of ixemul.library for the Amiga.
* Copyright (C) 1991, 1992 Markus M. Wild
*
* This library is free software; you can redistribute it and/or
* modify it under the terms of the GNU Library General Public
* License as published by the Free Software Foundation; either
* version 2 of the License, or (at your option) any later version.
*
* This library is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Library General Public License for more details.
*
* You should have received a copy of the GNU Library General Public
* License along with this library; if not, write to the Free
* Software Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
*
*/
#define KERNEL
#include "ixemul.h"
#include "kprintf.h"
#include <hardware/intbits.h>
#include <ctype.h>
#include <sys/wait.h>
#include <sys/exec.h>
#include "atexit.h"
#define __atexit (u.u_atexit)
#define alloca __builtin_alloca
#define JMP_MAGIC_16(code) ((code[0] & 0xffff0000) == 0x4efa0000)
#define JMP_MAGIC_32(code) ((code[0] & 0xffff0000) == 0x4efb0000)
#define JRA_MAGIC_16(code) ((code[0] & 0xffff0000) == 0x60000000)
#define MAGIC_16(code) \
((JMP_MAGIC_16 (code) || JRA_MAGIC_16 (code)) && \
(code[1] & 0xffff) == OMAGIC)
#define MAGIC_32(code) \
(JMP_MAGIC_32 (code) && (code[2] & 0xffff) == OMAGIC)
extern void bcopy (void *, void *, int);
extern BPTR *__load_seg (const char *name, char **args);
extern void __free_seg (BPTR *segs);
extern void *kmalloc (size_t);
extern void *krealloc (void *, size_t);
extern char *index (const char *, int);
extern char *strpbrk (const char *, const char *);
extern void kfree (void *);
extern char *strcpy (char *, const char *);
extern void all_free (void);
static int compatible_startup (void *code, int argc, char **argv);
static char *quote (char *orig);
static void volatile on_real_stack (BPTR *segs, char **argv, char **environ, int omask);
BPTR dup2_BPTR (int);
void readargs_kludge (BPTR);
int
execve (char *path, char **argv, char **environ)
{
BPTR *segs;
u_int omask, err;
char *extra_args = 0;
KPRINTF (("execve (%s,...)\n", path));
KPRINTF_ARGV ("argv", argv);
KPRINTF_ARGV ("environ", environ);
omask = syscall (SYS_sigsetmask, ~0);
segs = __load_seg (path, &extra_args);
if (segs && segs != (BPTR *)-2)
{
/* Now it gets somewhat nasty... since I have to revert to the `real'
stack (since the parent will want its sp back ;-)), I have to save
the values of this stack frame into registers, or I'll never be
able to access them afterwards again.. */
register BPTR *_segs asm ("d2");
register char **_argv asm ("d3");
register char **_environ asm ("d4");
/* if we got extra arguments, split them into a 2 el argument vector, and join
* `argv' */
if (extra_args && *extra_args)
{
char **ap, **nargv;
int size;
for (size = 0, ap = argv; *ap; size++, ap++) ;
nargv = (char **) syscall (SYS_malloc, (size + 4) * 4);
ap = nargv;
*ap++ = *argv++; /* keep the program name */
*ap++ = extra_args;
*ap = index (extra_args, ' ');
if (*ap)
{
**ap = 0;
++*ap;
++ap;
}
while (*ap++ = *argv++) ;
argv = nargv;
}
_segs = segs;
_argv = argv;
_environ = environ;
#ifndef USE_VFORK_RESUME
KPRINTF (("execve: about to call on_real_stack ()\n"));
if (u.p_vfork_msg)
{
set_sp ((u_int) u.u_save_sp);
/* fool the optimizer... */
asm volatile ("" : "=g" (_segs), "=g" (_argv), "=g" (_environ) : "0" (_segs), "1" (_argv), "2" (_environ));
KPRINTF (("execve () restored native sp\n"));
}
#else
/* this option is currently not recommended. execve needs to allocate memory
later on, and this should not happen inside Forbid! */
Forbid ();
vfork_resume ();
#endif
on_real_stack (_segs, _argv, _environ, omask);
/* never reached */
}
err = ENOENT;
syscall (SYS_sigsetmask, omask);
errno = err;
KPRINTF (("&errno = %lx, errno = %ld\n", &errno, errno));
return -1;
}
char **
dupvec (char **vec)
{
int n;
char **vp, **res;
static char *empty[] = { NULL };
if (! vec)
return empty;
for (n = 0, vp = vec; *vp; n++, vp++) ;
/* contrary to `real' vfork(), malloc() works in the child on its own
data, that is it won't clobber anything in the parent */
res = (char **) syscall (SYS_malloc, (n + 1) * 4);
if (res)
{
for (vp = res; n-- > 0; vp++, vec++)
*vp = (char *) syscall (SYS_strdup, *vec);
*vp = 0;
}
return res;
}
static void volatile
on_real_stack (BPTR *segs, char **argv, char **environ, int omask)
{
int private_startup;
u_int *code;
int (*entry) (struct ixemul_base *, int, char **, char **);
struct exec *hdr;
int f;
jmp_buf old_exit;
u_int old_a4 = 0;
KPRINTF (("entered on_real_stack()\n"));
/* first make sure that we're later passing on `safe' data to our child, ie.
copy it from wherever the data is currently stored into child malloc space */
vfork_own_malloc ();
if (environ)
*u.u_environ = dupvec(environ);
environ = *u.u_environ;
argv = dupvec (argv);
KPRINTF_ARGV ("copy of argv", argv);
code = BTOCPTR (*segs);
code ++; /* code starts at offset 4 */
/* Check whether this program has our magic header. See crt0.c for details. */
if (MAGIC_16 (code))
{
private_startup = 1;
hdr = (struct exec *) &code[1];
}
else if (MAGIC_32 (code))
{
private_startup = 1;
hdr = (struct exec *) &code[2];
}
else
{
private_startup = 0;
}
KPRINTF (("magic header %s\n", private_startup ? "found" : "NOT found"));
KPRINTF (("code[0] = %lx; code[1] = %lx; code[2] = %lx\n", code[0], code[1], code[2]));
#if 0
{
char **cp;
KPRINTF (("execve ["));
for (cp = argv; *cp; cp++) KPRINTF (("%s%s", *cp, cp[1] ? ", " : "], ["));
for (cp = environ; *cp; cp++) KPRINTF (("%s%s", *cp, cp[1] ? ", " : "]\n"));
}
#endif
if (private_startup)
{
entry = (void *) hdr->a_entry;
if (! entry) private_startup = 0;
}
/* okay, get ready to turn us into a new process, as much as
we can actually.. */
/* close all files with the close-on-exec flag set */
for (f = 0; f < NOFILE; f++)
{
if (u.u_ofile[f] && (u.u_pofile[f] & UF_EXCLOSE))
syscall (SYS_close, f);
}
/* BIG question what to do with registered atexit() handlers before
an exec.. Unix for sure does nothing, since the process space is
physically written over. In the AmigaDOS I could (!) imagine
cases where calling some atexit() handlers (mostly in the case
of destructors for C++ objects) would result in erronous
behaving of the program. However, since atexit() handlers also
serve to get rid of acquired Amiga resources, I morally feel
obliged to call the handlers.. lets see if this results in
incompatibilities with programs that expect Unix behavior. (Note
that I don't call exit() after exeve() returns, I call _exit(),
and _exit() does not walk the atexit() list).
There is one special case that I catch here, this is stdio. No
Unix program would ever expect stdio buffers to be flushed by
an execve() call. So since stdio is in the library I know the
address of the handler to skip ;-)) */
while (__atexit)
{
while (__atexit->ind --)
{
/* this is the stdio function to flush all buffers */
extern void _cleanup();
if (__atexit->fns[__atexit->ind] != _cleanup)
{
if (u.u_a4)
asm volatile ("movel %0, a4" : : "g" (u.u_a4));
__atexit->fns[__atexit->ind] ();
}
}
__atexit = __atexit->next;
}
/* `ignored signals remain ignored across an execve, but
signals that are caught are reset to their default values.
Blocked signals remain blocked regardless of changes to
the signal action. The signal stack is reset to be
undefined'. */
u.u_sigonstack = 0; /* default = on normal stack */
u.u_sigintr = 0; /* default = don't interrupt syscalls */
u.p_sigcatch = 0; /* no signals caught by user -> SIG_DFL */
for (f = 0; f < NSIG; f++) /* reset handlers to SIG_DFL, except for SIG_IGN */
if (u.u_signal[f] != SIG_IGN)
u.u_signal[f] = SIG_DFL;
/* what happens when we execute execve() from a signal handler
that executes on the signal stack? Better don't do this... */
/* deinstall our sigwinch input-handler */
ix_remove_sigwinch ();
/* save the original exit-jmpbuf, as ix_exec_entry() will destroy
* it later */
bcopy (u.u_jmp_buf, old_exit, sizeof (old_exit));
if (u.p_flag & SFREEA4)
{
old_a4 = u.u_a4;
u.p_flag &= ~SFREEA4;
}
/* count the arguments */
for (f = 0; argv[f]; f++) ;
KPRINTF (("found %ld args\n", f));
#ifndef USE_VFORK_RESUME
KPRINTF (("execve() having parent resume\n"));
if (u.p_vfork_msg)
{
/* make the parent runable again */
ReplyMsg ((struct Message *) u.p_vfork_msg);
u.p_vfork_msg = 0;
}
#else
Permit ();
#endif
KPRINTF (("execve() calling entry()\n"));
{
char *orig, **name;
struct Process *me = (struct Process *) FindTask (0);
struct CommandLineInterface *CLI = BTOCPTR (me->pr_CLI);
char *bcpl_argv0;
bcpl_argv0 = alloca (strlen (argv[0]) + 4);
bcpl_argv0 = LONG_ALIGN (bcpl_argv0);
if (CLI)
{
name = (char **) & CLI->cli_CommandName;
orig = *name;
bcpl_argv0[0] = strlen (argv[0]);
bcopy (argv[0], &bcpl_argv0[1], bcpl_argv0[0] + 1);
*name = (char *) CTOBPTR (bcpl_argv0);
}
else
{
name = (char **) & me->pr_Task.tc_Node.ln_Name;
orig = *name;
*name = argv[0];
}
u.u_oldmask = omask;
if (private_startup)
f = entry (ixemulbase, f, argv, environ);
else
f = compatible_startup (code, f, argv);
*name = orig;
}
__free_seg (segs);
if (old_a4)
{
u.u_a4 = old_a4;
u.p_flag |= SFREEA4;
}
KPRINTF (("old program doing _exit(%ld)\n", f));
/* and fake an _exit */
_longjmp (old_exit, f + 1);
}
/* some rather rude support to start programs that don't have a struct exec
* information at the beginning.
* 1.3 NOTE: This will only start plain C programs, nothing that smells like
* BCPL. Limited support for ReadArgs() style parsing is here, but not
* everything is set up that would have to be set up for BCPL programs
* to feel at home. Also don't use Exit() in those programs, it wouldn't
* find what it expects on the stack....
*/
static int
compatible_startup (void *code, int argc, char **argv)
{
char *al;
int max, res;
u_int oldsigalloc;
struct Process *me = (struct Process *) FindTask (0);
KPRINTF (("entered compatible_startup()\n"));
KPRINTF (("argc = %ld\n", argc));
KPRINTF_ARGV ("argv", argv);
/* ignore the command name ;-) */
argv++;
max = 1024;
al = (char *) kmalloc (max);
res = -1;
if (al)
{
char *cp;
register int d0 asm ("d0");
register char *a0 asm ("a0");
register void *a1 asm ("a1");
BPTR old_cis, old_cos, old_ces;
BPTR dup_cis, dup_cos, dup_ces;
void *old_trapdata, *old_trapcode;
int old_flags;
void *old_launch, *old_switch;
struct file *f;
for (cp = al; *argv; )
{
char *newel = quote (*argv);
int elsize = strlen (newel ? newel : *argv) + 2;
KPRINTF (("arg [%s] quoted as [%s]\n", *argv, newel ? newel : *argv));
if (cp + elsize >= al + max)
{
char *nal;
max <<= 1;
nal = (char *) krealloc (al, max);
if (! nal) break;
cp = nal + (cp-al);
al = nal;
}
strcpy (cp, newel ? newel : *argv);
cp += elsize - 2;
*cp++ = ' ';
*cp = 0;
if (newel) kfree (newel);
++argv;
}
/* BCPL weirdness ... */
*cp++ = '\n';
*cp = 0;
KPRINTF (("BCPL cmd line = [%s]\n", al));
/* problem with RunCommand: the allocated signal mask is not reset
for the new process, thus if several RunCommands are nested, a
late started process might run out of signals. This behavior makes
no sense, since the starting process is *suspended* while the `child'
is running, thus it doesn't need its signals in the meantime ! */
oldsigalloc = me->pr_Task.tc_SigAlloc & 0xffff0000; /* hacky...*/
me->pr_Task.tc_SigAlloc &= 0xffff;
/* cleanup as much of ixemul.library as possible, so that the started
process can take over */
old_flags = me->pr_Task.tc_Flags;
me->pr_Task.tc_Flags = u_save.u_otask_flags;
old_launch = me->pr_Task.tc_Launch;
me->pr_Task.tc_Launch = u_save.u_olaunch; /* restoring this disables our signals */
old_switch = me->pr_Task.tc_Switch;
me->pr_Task.tc_Switch = u_save.u_oswitch;
RemIntServer (INTB_VERTB, & u_save.u_itimerint);
#if 0
/* looks like we shouldn't do this, bus errors are the consequence.. */
/* free the task private malloc'd data */
all_free ();
#endif
/* limited support (part 2 ;-)) for I/O redirection on old programs
If we're redirecting to a plain file, don't go thru a IXPIPE,
temporarily use our DOS files in that case. Any other file type
is routed thru an IXPIPE though. */
if ((f = u_save.u_ofile[0]) && f->f_type == DTYPE_FILE)
{
dup_cis = 0;
old_cis = SelectInput (CTOBPTR (f->f_fh));
readargs_kludge (CTOBPTR (f->f_fh));
}
else
{
if (!f)
{
int fd = open ("/dev/null", 0);
dup_cis = dup2_BPTR (fd);
close (fd);
}
else
dup_cis = dup2_BPTR (0);
old_cis = 0;
if (dup_cis)
{
old_cis = SelectInput (dup_cis);
readargs_kludge (dup_cis);
}
}
if ((f = u_save.u_ofile[1]) && f->f_type == DTYPE_FILE)
{
dup_cos = 0;
old_cos = SelectOutput (CTOBPTR (f->f_fh));
}
else
{
if (!f)
{
int fd = open ("/dev/null", 1);
dup_cos = dup2_BPTR (fd);
close (fd);
}
else
dup_cos = dup2_BPTR (1);
old_cos = 0;
if (dup_cos)
old_cos = SelectOutput (dup_cos);
}
old_ces = me->pr_CES;
if ((f = u_save.u_ofile[2]) && f->f_type == DTYPE_FILE)
{
dup_ces = 0;
me->pr_CES = CTOBPTR (f->f_fh);
}
else
{
if (!f)
{
int fd = open ("/dev/null", 2);
dup_ces = dup2_BPTR (fd);
close (fd);
}
else
dup_ces = dup2_BPTR (2);
me->pr_CES = dup_ces ? : old_ces;
}
/* BEWARE that after this reset no library functions can be
called any longer until the moment where trapdata is
reinstalled !! */
old_trapdata = me->pr_Task.tc_TrapData;
me->pr_Task.tc_TrapData = u_save.u_otrap_data;
old_trapcode = me->pr_Task.tc_TrapCode;
me->pr_Task.tc_TrapCode = u_save.u_otrap_code;
{
struct CommandLineInterface *CLI = BTOCPTR (me->pr_CLI);
u_int stack_size = CLI ? CLI->cli_DefaultStack * 4 : me->pr_StackSize;
/* perhaps someone really uses so small stacks......... */
/* if (stack_size <= 4096) stack_size = 250000; */
/* the above approach has too many incompatibilities, sigh.
Note: The use of RunCommand() here means, that we *waste* the
entire stack space allocated for this process! If someone
comes up with a clever trick (probably involving StackSwap ())
where the stack of this process can be freed before calling
RunCommand (), lots of users with memory problems would be
thankful! */
res = RunCommand (CTOBPTR (code) - 1, stack_size, al, cp - al);
}
/* reinstall enough of ixemul to be able to finish cleanly
(the recent addition of an ix_sleep() at the end of a vfork'd
process makes it necessary to reinstall the signalling facilities!) */
me->pr_Task.tc_TrapData = old_trapdata;
me->pr_Task.tc_TrapCode = old_trapcode;
/* have to do this, or ix_close() is not able to RemoveIntServer .. */
AddIntServer (INTB_VERTB, & u_save.u_itimerint);
me->pr_Task.tc_Launch = old_launch;
me->pr_Task.tc_Switch = old_switch;
me->pr_Task.tc_Flags = old_flags;
kfree (al);
if (old_cis)
SelectInput (old_cis);
if (old_cos)
Flush (SelectOutput (old_cos));
me->pr_CES = old_ces;
if (dup_cis)
Close (dup_cis);
if (dup_cos)
Close (dup_cos);
if (dup_ces)
Close (dup_ces);
me->pr_Task.tc_SigAlloc |= oldsigalloc;
}
return res;
}
static char *
quote (char *orig)
{
int i;
char *new, *cp;
i = strlen (orig);
if (strpbrk (orig, "\"\'\\ \t\n"))
{
/* worst case, each character needs quoting plus starting and ending " */
new = (char *) kmalloc (i * 2 + 3);
if (! new) return 0;
cp = new;
*cp++ = '"';
while (*orig)
{
if (index ("\"\\", *orig))
*cp++ = '\\';
*cp++ = *orig++;
}
*cp++ = '"';
*cp = 0;
return new;
}
else
return 0; /* means `just use the original string' */
}
/* try to obtain a DOS filehandle on the specified descriptor. This only
works, if the user has mounted IXPIPE: */
BPTR
dup2_BPTR (int fd)
{
long id;
char name[20];
id = fcntl (fd, F_EXTERNALIZE, 0);
if (id >= 0)
{
sprintf (name, "IXPIPE:%x", id);
/* 0x4242 is a magic packet understood by IXPIPE: to F_INTERNALIZE id */
return Open (name, 0x4242);
}
return 0;
}
/* the mysteries of DOS seem to never want to take an end... */
void
readargs_kludge (BPTR bp)
{
int ch;
static const int EOS_CHAR = -1;
#if 0
/* the autodocs say this bug is fixed after v37, well, perhaps that was a
very deep wish, nevertheless unheard by dos...
Without this kludge, you have to actually press return if stdin is not
redirected...
Thanks mbs: without your shell code I would never have guessed that
something that weird could be possible....
*/
if (ix.ix_dos_base->lib_Version <= 37)
#endif
{
ch = UnGetC (bp, EOS_CHAR) ? 0 : '\n';
while ((ch != '\n') && (ch != EOS_CHAR))
ch = FGetC (bp);
Flush (bp);
}
}